home *** CD-ROM | disk | FTP | other *** search
/ Libris Britannia 4 / science library(b).zip / science library(b) / DDJMAG / DDJ9006.ZIP / GESSNER.LST < prev    next >
File List  |  1990-05-02  |  30KB  |  635 lines

  1. _BUILDING A HYPERTEXT SYSTEM_
  2. by Rick Gessner
  3.  
  4. [LISTING ONE]
  5.  
  6.  {$V-} {$F+} {$O+}   { Written By:  Rick Gessner, 1989. }
  7.  
  8.  Unit HyprText;
  9.  {-------} Interface {-----------------------------------------------}
  10.  
  11.  PROCEDURE Help_Editor(FileName: String);
  12.  PROCEDURE Do_help(FileName: String; GoPage,HomePage: Word);
  13.  {-------} Implementation {------------------------------------------}
  14.  Uses Crt;
  15.  
  16.  CONST HelpColor        : Array[False..true] of Byte =
  17.                              ( Black*16+White,     {Used for normal text}
  18.                                Magenta*16+Yellow); {Used for hot-link text.}
  19.        NormalColor      : Byte = Black*16+White;   {Used to draw screen info.}
  20.        BoldColor        : Byte = White*16+Black-Blink;  {Used for select bar.}
  21.        Header           : String[50] = ' HyperText System [1.0] ';
  22.        MaxLinesPerPage  = 15;
  23.        MaxLineWidth     = 57;
  24.  
  25.        PGUP    = 'I';      PGDN    = 'Q';      UpArrow = 'H'; {Edit keys}
  26.        DnArrow = 'P';      LArrow  = 'K';      RArrow  = 'M';
  27.        ESC     = #27;      HomeKey = 'G';      EndKey  = 'O';
  28.        RETURN  = ^M;       BkSpc   = #8;       NULL    = #0;
  29.        Tab     = #9;       F2      = '<';      DelKey  = 'S';
  30.  Type  HelpRecord = Record  {The main structure for our hypertext files}
  31.            HelpLines : Array[1..MaxLinesPerPage] of String[100];
  32.        end; {String length MUST be > than MaxLineWidth to store hot-links!}
  33.  Var   HelpRec    : HelpRecord;
  34.        HelpFile   : File of HelpRecord;
  35.        Alt,Ctrl,CommandKey : Boolean;
  36. {--------------------------------------------------------------------}
  37.  FUNCTION Make_String(Ch   : Char; Size : Integer) : String;
  38.  Var S: string;
  39.  Begin
  40.      S[0] := Chr(Size);                  { Set length byte = SIZE.          }
  41.      FillChar(S[1],Size,Ch);             { Fill the string with chr(CH).    }
  42.      Make_String:= S;                    { and return the string as function}
  43.  end; {Make String }                     { value.                           }
  44. {--------------------------------------------------------------------}
  45.  PROCEDURE Draw_Box(topx,topy,botx,boty: Byte; Color,Width: byte);
  46.  Type BoxPos = (TopL,TopR,BotL,BotR,Top,Bot,LSide,RSide);
  47.  Var Y       : Integer;
  48.  Const  Boxchar : Array[1..2,TopL..RSide] of char =
  49.     (( 'Z','?','@','Y','D','D','3','3'),  { ASCII chars for single line box }
  50.      ( 'I',';','H','<','M','M',':',':')); { ASCII chars for double line box }
  51.  Begin
  52.    TextAttr:=Color;
  53.    If Not (Width in [1,2]) then Width:=1; { Make sure width value is OK   }
  54.    Gotoxy(TopX,TopY);    { First, draw the top line of the box...}
  55.    Write( BoxChar[Width,TopL]+Make_String(BoxChar[width,top],BotX-TopX-1)+
  56.                                                         BoxChar[Width,TopR]);
  57.    For Y:=TopY+1 to BotY-1 do
  58.    Begin                 { Second, draw the middle lines of the box...}
  59.            Gotoxy(TopX,Y);
  60.            Write( BoxChar[Width,LSide],BoxChar[Width,RSide]:BotX-TopX);
  61.    end;
  62.    GotoXY(TopX,BotY);    { Third, draw the bottom line of the box. }
  63.    Write( BoxChar[Width,BotL]+Make_String(BoxChar[width,top],BotX-TopX-1)+
  64.                                                          BoxChar[Width,BotR])
  65.  end; {Draw Box}
  66. {--------------------------------------------------------------------}
  67.  FUNCTION Read_KeyBoard: Char;   {Routine to get keystrokes from user}
  68.  Const  CtrlMask  = $04;
  69.         AltMask   = $08;
  70.  Var    KBDFlag   : Byte Absolute $0040:$0017;
  71.  Begin
  72.   Read_KeyBoard:=ReadKey;
  73.   CommandKey := ((KBDFlag AND AltMask) <> 0) or ((KBDFlag AND CtrlMask) <> 0);
  74.   ALT  := (KBDFlag AND AltMask) <> 0; CTRL := (KBDFlag AND CtrlMask) <> 0;
  75.   If KeyPressed Then
  76.   Begin
  77.           Read_Keyboard := ReadKey; {Just in case user pressed modified key}
  78.           CommandKey := True;
  79.    end;
  80.  end; {Read_Keyboard}
  81. {--------------------------------------------------------------------}
  82.   PROCEDURE Show_HelpLine(X,Y,StartBold,EndBold: Integer; Var Line: String);
  83.   Var I,J: Integer;
  84.        PROCEDURE Write_Char(Ch: Char);
  85.        Begin
  86.             If Ord(Ch)>127 then Ch:=Chr(Ord(Ch)-128); {Clear high bit}
  87.             If Ord(Ch)>27 then Write(Ch) else Inc(i);
  88.        end;
  89.   Begin
  90.        TextAttr:=HelpColor[False];
  91.        Window(X,Y,59,Y); ClrEOL; Window(1,1,80,25); {Prepare for output}
  92.        Gotoxy(X,Y); I:=1;
  93.        While I<=Length(Line) do                       {Do each char in line}
  94.        Begin
  95.             TextAttr:=HelpColor[Ord(Line[i])>128];    {Set proper color}
  96.             If I in [StartBold..EndBold] then TextAttr:=BoldColor;
  97.             Write_Char(Line[i]);
  98.             Inc(i);
  99.        end;
  100.   end; {Show helpline}
  101.  {-------------------------------------------------------------------}
  102.   PROCEDURE Show_Help_Page(X,Y: Integer; Var HelpRec: HelpRecord);
  103.   Var I: Integer;
  104.   Begin
  105.        Window(X+1,Y+1,X+56,Y+MaxLinesPerPage+1); ClrScr; Window(1,1,80,25);
  106.        For I:=1 to MaxLinesPerPage do
  107.            Show_HelpLine(X,Y+I,0,0,HelpRec.HelpLines[I]);
  108.   end; {Show help page}
  109.  {-------------------------------------------------------------------}
  110.   FUNCTION Determine_Actual_Line_Pos(Var Line: String; LinePos: Integer): 
  111.                                                                      Integer;
  112.   Var I,J: Integer;  {Convert visual edit column to actual char. position,}
  113.   Begin              {by skipping over embedded hot links.}
  114.        I:=0; J:=1;
  115.        While (J<=Length(Line)) and (I<>LinePos) do
  116.        Begin
  117.             If Line[j]<>Null then   {Null is used as delimiter}
  118.                Inc(i) else Inc(j,2);
  119.             Inc(j);
  120.        end;
  121.        Determine_Actual_Line_Pos:=J;
  122.   end; {Determine actual line pos}
  123.  {-------------------------------------------------------------------}
  124.   FUNCTION Link_Count(Var Line: String): Integer;
  125.   Var I,Count: Integer;  { Returns 2*#nulls in line, used to convert }
  126.   Begin                  { from actual byte pos. to visual byte pos., }
  127.        Count:=0;         { during data input. }
  128.        For I:=1 to Length(Line) do
  129.            If Line[i]=Null then Inc(Count,2);
  130.        Link_Count:=Count;
  131.   end; {Link count}
  132.  {-------------------------------------------------------------------}
  133.   FUNCTION Input_HelpPage(X,Y: Byte; Var AHelpRec: HelpRecord): Char;
  134.   Var   Ch          : Char;   { The main editing routine in this system.  }
  135.         PageNum     : Byte;   { It is really just a page-oriented line    }
  136.         I,J,                  { editor that knows how to jump over 2-byte }
  137.         LinePos,              { hot-links.                                }
  138.         RealLinePos,          { If you add editing options, don't forget  }
  139.         LineNum     : Integer;{ take the embedded hot-links into account! }
  140.  
  141.         PROCEDURE Delete_Linked_Char(Var Line: String; LinePos: Integer);
  142.         Var I,J: Integer;
  143.         Begin
  144.              LinePos:=Pred(Determine_Actual_Line_Pos(Line,LinePos));
  145.              If Ord(Line[LinePos])>127 then  {Were on a linked item}
  146.              Begin
  147.               I:=LinePos;
  148.               While ((Ord(Line[I-1])>127) and (I>1)) do Dec(i); 
  149.               J:=LinePos;                           {Next find end of link}
  150.                   While ((Ord(Line[J+1])>127) and (I<Length(Line))) do Inc(J);
  151.                   Delete(Line,LinePos,  {Delete all of item + link if necc.}
  152.                          1+(2*Ord(J=I)));
  153.              end;
  154.         end; {Delete linked char}
  155.   Begin
  156.        Show_Help_Page(X,Y,AHelpRec);  {Display this page }
  157.        LinePos:=1; RealLinePos:=1;    {Now do a little init stuff.}
  158.        LineNum:=1;
  159.        With AHelpRec do               {Now enter main edit loop...}
  160.        Repeat
  161.              Show_HelpLine(X,Y+LineNum,0,0,HelpLines[LineNum]);
  162.              Gotoxy(X+LinePos-1,Y+LineNum);
  163.              Repeat Ch:=Read_KeyBoard Until Ch <> Null;
  164.              If CommandKey then
  165.                 Case Ch of
  166.                  ^Y     : If RealLinePos<=Length(HelpLines[LineNum]) then
  167.                           Begin    { ^Y = Delete to end of line. }
  168.                              If (RealLinePos=1) then HelpLines[LineNum]:=''
  169.                              else
  170.                              Begin
  171.                                 While HelpLines[LineNum,RealLinePos]<>Null do
  172.                                  Delete(HelpLines[LineNum],RealLinePos,1);
  173.                                 If HelpLines[LineNum,RealLinePos]=Null then
  174.                                  Delete(HelpLines[LineNum],RealLinePos+2,255)
  175.                               end
  176.                          end;
  177.                  F2     : Begin { F2 = Add/Remove hot-link.}
  178.                                 J:=RealLinePos;
  179.                                 While (j>0) and (HelpLines[LineNum,j]<>' ') 
  180.                                                                    do Dec(j);
  181.                                 Inc(j);
  182.                                 If Ord(HelpLines[Linenum,j]) in [28..127] then
  183.                                 Repeat {Now get a valid page # to jump to...}
  184.                                      Gotoxy(3,24); Write('Link Page: ');
  185.                                      Readln(PageNum);
  186.                                      Gotoxy(3,24); ClrEOL;
  187.                                 Until (PageNum>0) and (PageNum<256);
  188.                                 While (HelpLines[LineNum,j]<>' ') and 
  189.                                          (j<=Length(HelpLines[LineNum])) and
  190.                                       (HelpLines[LineNum,j]<>Null) do
  191.                                 Begin
  192.                                      HelpLines[LineNum,j]:=Chr(Ord(HelpLines
  193.                                                            [LineNum,j])+128);
  194.                                      Inc(j);
  195.                                 end;
  196.                              If Ord(HelpLines[LineNum,J-1]) in [28..127] then 
  197.                              Delete(HelpLines[LineNum],J,2) else 
  198.                              Insert(Null+Chr(PageNum),HelpLines[LineNum],j);
  199.                            end;
  200.                  LArrow : If RealLinePos>1 then  {Move cursor left 1 char.}
  201.                        Begin
  202.                           Dec(linePos);
  203.                           RealLinePos:=Pred(Determine_Actual_Line_Pos
  204.                                               (HelpLines[LineNum],LinePos));
  205.                        end;
  206.                  RArrow : If RealLinePos<=Length(HelpLines[LineNum]) then
  207.                            Begin                 {Move cursor right 1 char.}
  208.                                 Inc(LinePos);
  209.                                 If RealLinePos<Length(HelpLines[LineNum]) then
  210.                                    Inc (RealLinePos,
  211.                                 1+Ord(HelpLines[LineNum,RealLinePos+1]=Null)*2)
  212.                                 else Inc(realLinePos)
  213.                            end;
  214.                  DnArrow: If LineNum<MaxLinesPerPage then
  215.                       Begin                 {Move down 1 line.}
  216.                          Inc(LineNum);
  217.                          If LinePos<=Length(HelpLines[LineNum]) then
  218.                            RealLinePos:=Pred(Determine_Actual_Line_Pos
  219.                                                (HelpLines[LineNum],LinePos))
  220.                          else
  221.                           Begin
  222.                            RealLinePos:=Succ(Length(HelpLines[LineNum]));
  223.                            LinePos:=RealLinePos-Link_Count(HelpLines[LineNum]);
  224.                           end;
  225.                       end;
  226.                  UpArrow: If LineNum>1 then      {Move up 1 line.}
  227.                       Begin
  228.                          Dec(LineNum);
  229.                          If LinePos<=Length(HelpLines[LineNum]) then
  230.                            RealLinePos:=Pred(Determine_Actual_Line_Pos
  231.                                                (HelpLines[LineNum],LinePos))
  232.                          else
  233.                         Begin
  234.                          RealLinePos:=Succ(Length(HelpLines[LineNum]));
  235.                          LinePos:=RealLinePos-Link_Count(HelpLines[LineNum]);
  236.                         end;
  237.                       end;
  238.                  HomeKey: Begin                 {Move to 1 char. in line.}
  239.                                 LinePos:=1;
  240.                                 RealLinePos:=LinePos;
  241.                            end;
  242.                  EndKey : Begin                 {Move to end of line.}
  243.                         RealLinePos:=Succ(Length(HelpLines[LineNum]));
  244.                         LinePos:=RealLinePos-Link_Count(HelpLines[LineNum]);
  245.                         end;
  246.                  DelKey : If (RealLinePos<=Length(HelpLines[LineNum])) then
  247.                         Begin                 {Delete a character.}
  248.                          If (HelpLines[LineNum,RealLinePos]) in [' '..'}'] 
  249.                            then Delete(HelpLines[LineNum],RealLinePos,1) else
  250.                          Delete_Linked_Char(HelpLines[LineNum],LinePos);
  251.                          RealLinePos:=Pred(Determine_Actual_Line_Pos
  252.                                               (HelpLines[LineNum],LinePos));
  253.                           end;
  254.                 end else
  255.                 Case Ch of
  256.                  Return: If LineNum<MaxLinesPerPage then  {Move down 1 line.}
  257.                           Begin
  258.                                Inc(LineNum); LinePos:=1; RealLinePos:=1;
  259.                           end;
  260.                     Tab : Begin    {Tab right 10 chars.}
  261.                         If RealLinePos+10<=Length(HelpLines[LineNum])+1 then
  262.                                Inc(RealLinePos,10) else
  263.                          RealLinePos:=Length(HelpLines[LineNum])+1;
  264.                          LinePos:=RealLinePos-Link_Count(HelpLines[LineNum]);
  265.                            end;
  266.                   BkSpc  : If RealLinePos>1 then  {Backspace over prev. char.}
  267.                        Begin
  268.                         If HelpLines[LineNum,RealLinePos-1] in [' '..'}'] then
  269.                               Begin
  270.                                   Delete(HelpLines[LineNum],RealLinePos-1,1); 
  271.                                   Dec(RealLinePos);
  272.                                   Dec(LinePos)
  273.                               end else
  274.                           Begin
  275.                             Delete_Linked_Char(HelpLines[LineNum],LinePos-1);
  276.                                   Dec(LinePos);
  277.                                   RealLinePos:=Pred(Determine_Actual_Line_
  278.                                            Pos(HelpLines[LineNum],LinePos));
  279.                                 end;
  280.                           end;
  281.                ' '..'}' : If Length(HelpLines[LineNum])<MaxLineWidth then
  282.                            Begin     {Insert a valid Ascii char.}
  283.                             If (Ord(HelpLines[LIneNum,RealLinePos])>127) and
  284.                                (RealLinePos<=Length(HelpLines[Linenum])) then
  285.                                  Ch:=Chr(Ord(Ch)+128);
  286.                              Insert(Ch,HelpLines[LineNum],RealLinePos);
  287.                              Inc(RealLinePos);
  288.                              Inc(LinePos); Ch:=#255;
  289.                            end;
  290.              end;
  291.        Until CH in [ESC,PGUp,PgDn]; {ESC=Quit;PGUp=Prev page;PgDn=Next Page.}
  292.        Input_HelpPage:=Ch;
  293.   end; {Input helppage}
  294. {--------------------------------------------------------------------}
  295.   FUNCTION Read_Helprec(Var AHelpRec: HelpRecord; RecNum: Integer ): Integer;
  296.   Var I : Integer;
  297.   Begin
  298.        FillChar(AHelprec,SizeOf(AHelprec),0); {$I-} {Hyperdata file read rec}
  299.        If FileSize(HelpFile)<RecNum then exit;      {routine. Includes just }
  300.        Seek(helpfile,RecNum-1);                     {enough error checking  }
  301.        Read(helpfile,AHelpRec);                     {to be considered safe. }
  302.        Read_HelpRec:=IOResult; {$I+}
  303.   end; {Read helprec}
  304. {--------------------------------------------------------------------}
  305.   FUNCTION Write_HelpRec(Var AHelpRec: HelpRecord; RecNum: Integer): Integer;
  306.   Begin {$I-}
  307.        Seek(helpfile,RecNum-1);         {Hyperdata file write rec routine.}
  308.        Write(helpfile,AHelpRec); {$I+}  {This routine also contains just  }
  309.        Write_HelpRec:=IOresult;         {enough error checking to be      }
  310.   end; {Write helprec}                  {considered safe.                 }
  311. {--------------------------------------------------------------------}
  312.   FUNCTION Open_HelpFile(FileName: String): Integer;
  313.   Var result: Integer;
  314.   Begin
  315.        Assign(HelpFile,FileName); {$I-}  {Opens hyperdata file specified}
  316.        Reset(HelpFile);                  {as "FileName".  If the file   }
  317.        result:=IOResult;                 {doesnt exist, then it will be }
  318.        If Result=2 then                  {created.                      }
  319.        Begin                             {Error checking is limited, but}
  320.             ReWrite(HelpFile);           {enough to be safe.            }
  321.             Result:=IOResult;
  322.        end;
  323.        Open_HelpFile:=Result;
  324.   end; {open helpfile}
  325. {--------------------------------------------------------------------}
  326.  PROCEDURE Help_Editor(FileName: String);
  327.  Const  HelpMsgs  = 13;
  328.         HelpData  : Array[1..HelpMsgs] of String[17] =
  329.                  ( 'Editing Keys: ',          '-------------',
  330.                    'F2   : Link (+/-)',       '^Y   : Del EOLine',
  331.                    'Bkspc: Del left',         'Del  : Del char',
  332.                    Chr(10)+'Movement keys: ', '--------------',
  333.                    Chr(24)+Chr(25)+Chr(27)+Chr(26)+', '+Chr(17)+Chr(217)+',',
  334.                    'Tab, Home, End',          'PgUp : Prev page',
  335.                    'PgDn : Next page',        Chr(10)+'ESC to quit.');
  336.  Var I,HelpRecNum: Integer;
  337.      AHelpRec    : HelpRecord;
  338.      Ch          : Char;
  339.      Result      : Integer;
  340.  Begin
  341.       Result:=Open_HelpFile(FileName);     {Open the specified file.}
  342.       If Result=0 then                     {Continue only if no error.}
  343.       Begin
  344.            TextAttr := NormalColor;
  345.            Draw_Box(1,3,80,23,NormalColor,1);
  346.            Draw_Box(2,4,60,22,NormalColor,2);
  347.            Gotoxy(61,4);
  348.            For I:=1 to HelpMsgs do
  349.            Begin
  350.                 Gotoxy(62,WhereY+1); Write(HelpData[i]);
  351.            end;
  352.            HelpRecNum:=1;
  353.            Gotoxy(40-(Length(Header) div 2),3); Writeln(Header);
  354.            Gotoxy(4,2); Writeln('File: ',FileName);
  355.            Repeat
  356.                  Gotoxy(4,4); Writeln(' Reading  ');
  357.                  Result:=Read_HelpRec(AHelpRec,HelpRecNum);
  358.                  Gotoxy(4,4); Writeln('Page: ',HelpRecNum:3);
  359.                   Ch:=Input_HelpPage(3,4,AHelpRec);
  360.                  Result:=Write_HelpRec(AHelpRec,HelpRecNum);
  361.                  Gotoxy(4,4); Writeln(' Writing  ');
  362.                  Case Ch of
  363.                       PgUp : If helpRecNum>1 then Dec(HelpRecNum);
  364.                       PgDn : If HelpRecNum < 255 then Inc(HelpRecNum);
  365.                  end;
  366.            Until Ch=ESC;
  367.      end else  {Report the opening error...}
  368.       Writeln('ERROR: ',Result,' opening ',FileName,'. Unable to continue.');
  369.      {$I-} Close(HelpFile); Result:=IOresult; {$I+}
  370.  end; {Help editor}
  371. {--------------------------------------------------------------------}
  372.  FUNCTION Find_Next_Link( Var X,Y: Integer; EndX,EndY: Integer;
  373.                           Var AHelpRec: HelpRecord): Boolean;
  374.  Var OrigX,OrigY,Col,                {Recursive routine used to find a }
  375.      Row,StartCol,StopCol: Integer;  {hot-link on the page after the   }
  376.  Begin                               {current page position (X,Y).     }
  377.       Find_Next_Link:=False;
  378.       {First, search from current pos to end of page...}
  379.       For Row:=Y to EndY do
  380.       Begin
  381.            If Row<>Y then StartCol:=1 else StartCol:=X;
  382.            If Row<>EndY then StopCol:=Length(AhelpRec.HelpLines[Row])
  383.               else StopCol:=EndX;
  384.            If AhelpRec.HelpLines[Row]<>'' then
  385.            For Col:=StartCol to StopCol do
  386.                If (AHelpRec.HelpLines[Row,Col]=Null) then
  387.                Begin
  388.                     Find_Next_Link:=True;
  389.                     X:=Col; Y:=Row;
  390.                     Exit;  {make a quick getaway!}
  391.                end;
  392.       end;
  393.       {ok, search from top of page to the startpos}
  394.       If X+Y>2 then
  395.       Begin
  396.            Col:=1; Row:=1;
  397.            If Find_Next_link(Col,Row,Pred(X),Y,AHelpRec) then
  398.            Begin
  399.                 X:=Col; Y:=Row; Find_Next_Link:=true;
  400.            end
  401.       end;
  402.  end; {find next link}
  403. {--------------------------------------------------------------------}
  404.  FUNCTION Find_Prev_Link( Var X,Y: Integer; EndX,EndY: Integer;
  405.                           Var AHelpRec: HelpRecord): Boolean;
  406.  Var OrigX,OrigY,Col,                 {Recursive routine used to find a }
  407.      Row,StartCol,StopCol: Integer;   {hot-link on the page prev. to the}
  408.  Begin                                {current page pos. (X,Y).         }
  409.       Find_Prev_Link:=False;
  410.       {First, search from current pos to top of page...}
  411.       For Row:=Y downto 1 do
  412.       Begin
  413.            StopCol:=1;
  414.            If Row<>Y then StartCol:=Length(AhelpRec.HelpLines[Row])
  415.               else StartCol:=X;
  416.            If AhelpRec.HelpLines[Row]<>'' then
  417.            For Col:=StartCol downto StopCol do
  418.                If (AHelpRec.HelpLines[Row,Col]=Null) then
  419.                Begin
  420.                     Find_Prev_Link:=True;
  421.                     X:=Col; Y:=Row;
  422.                     Exit;  {make a quick getaway!}
  423.                end;
  424.       end;
  425.       {ok, search from bottom of page to the startpos}
  426.       If X+Y>2 then
  427.       Begin
  428.            Row:=MaxLinesPerPage;
  429.            Col:=Length(AHelpRec.HelpLines[Row]);
  430.            If Find_Prev_link(Col,Row,Succ(X),Y,AHelpRec) then
  431.            Begin
  432.                 X:=Col; Y:=Row; Find_Prev_Link:=true;
  433.            end
  434.       end;
  435.  end; {find prev link}
  436. {--------------------------------------------------------------------}
  437.  PROCEDURE Do_Help(FileName: String; GoPage,HomePage: Word);
  438.  Const XPos = 10;
  439.        YPos = 5;
  440.        Color    : Byte = Black*16+White;   {This is the hypertext engine.}
  441.        MaxStackSize = 25;                  {This routine is used to read }
  442.                                            {and navigate through a data  }
  443.  Type  StackRec = Record                   {file, specfied as "FILENAME".}
  444.             Page : Byte;                   {GoPage specifies the starting}
  445.             Row,                           {page to display, and HomePage}
  446.             Col  : Integer;                {is used to specify an main   }
  447.        end;                                {index (or home) page.        }
  448.  Var   Result  : Integer;
  449.        Stack   : Array[0..MaxStackSize] of StackRec;
  450.        AHelpRec: HelpRecord;
  451.        Ch      : CHar;
  452.        StackLvl: Byte;
  453.        StartCol: Integer;
  454.        Linked,
  455.        Load    : Boolean;
  456.        FUNCTION Pop_Stack: Byte;  {Pop the top page info (Stack) record}
  457.        Begin
  458.             If StackLvl>1 then
  459.             Begin
  460.                  Dec(StackLvl);
  461.                  Load:=True;
  462.             end;
  463.             Pop_Stack:=StackLvl;
  464.        end; {pop stack}
  465.        FUNCTION Push_Stack(PageNum: Byte): Byte;
  466.        Begin                               {Push a page info (stack) record.}
  467.             Inc(StackLvl);
  468.             Stack[StackLvl].Page:=PageNum;
  469.             Stack[StackLvl].Col:=1;
  470.             Stack[StackLvl].Row:=1;
  471.             Push_Stack:=StackLvl;
  472.        end; {push stack}
  473.  Begin
  474.       If GoPage=0 then GoPage:=1;      {Make sure GoPage is valid.}
  475.       Result:=Open_HelpFile(FileName);
  476.       If Result=0 then
  477.       Begin
  478.            Load:=true;
  479.            TextAttr :=Color;
  480.            Draw_Box(Xpos,YPos,XPos+59,YPos+MaxLinesPerPage+2,NormalColor,2);
  481.            FillChar(Stack,SizeOf(Stack),0);
  482.            StackLvl := 0;
  483.            If HomePage in [1..255] then StackLvl:=Push_Stack(HomePage);
  484.            If (GoPage in [1..255]) and (GoPage<>HomePage) then 
  485.                                               StackLvl:=Push_Stack(GoPage);
  486.            GotoXY(XPos+29-(Length(Header) div 2),YPos);
  487.            Writeln(Header);
  488.            Repeat
  489.                  With Stack[StackLvl] do
  490.                  Begin
  491.                       If Load then  {System needs new hyperdata file page.}
  492.                       Begin
  493.                            Result:=Read_HelpRec(AHelpRec,Page);
  494.                            Show_Help_Page(XPos+1,YPos,AHelpRec);
  495.                            Gotoxy(XPos+51,YPos+MaxLinesPerPage+2);
  496.                            If StackLvl>1 then Write('Esc,PgUp') else 
  497.                                                          Write('Esc=Quit');
  498.                            Linked:=Find_Next_Link(Col,Row,80,MaxLinesPerPage,
  499.                                                                  AHelpRec);
  500.                            Load:=False;
  501.                       end;
  502.                       If Linked then {We have a hot-link to show, so do it.}
  503.                     Begin
  504.                            StartCol := Col;
  505.                            While Ord(AHelprec.HelpLines[Row,StartCol-1])>127 
  506.                                                            do Dec(StartCol);
  507.                            Show_HelpLine(XPos+1,YPos+Row,StartCol,Pred(Col),
  508.                                                    AHelpRec.HelpLines[Row]);
  509.                     end;
  510.                  Repeat Ch:=Read_KeyBoard until Ch<>Null;
  511.                  Show_HelpLine(XPos+1,YPos+Row,0,0,AHelpRec.HelpLines[Row]);
  512.                  Case Ch of   {Now handle navigation...}
  513.                            RArrow,
  514.                            Tab    : Begin
  515.                                          Inc(Col);
  516.                                          Linked:=Find_Next_Link(Col,Row,80,
  517.                                                    MaxLinesPerPage,AHelpRec);
  518.                                     end;
  519.                            Return : If Linked then
  520.                                Begin
  521.                                  Load:=true;
  522.                                   If (StackLvl>1) and  
  523.                                    (Stack[StackLvl-1].Page=
  524.                                      Ord(AHelpRec.HelpLines[Row,Col+1])) then
  525.                                        StackLvl:=Pop_Stack else
  526.                                  StackLvl:=Push_Stack(Ord(AHelpRec.HelpLines
  527.                                                                 [Row,Col+1]));
  528.                                end;
  529.                            LArrow : Begin
  530.                                Dec(Col);
  531.                                Linked:=Find_Prev_Link(Col,Row,1,1,AHelpRec);
  532.                                end;
  533.                            DnArrow: Begin
  534.                             Col:=1;
  535.                             If Row<MaxLinesPerPage then Inc(Row) else Row:=1;
  536.                             Linked:=Find_Next_Link(Col,Row,80,
  537.                                                    MaxLinesPerPage,AHelprec);
  538.                               end;
  539.                            UpArrow: Begin
  540.                             If Row>1 then Dec(Row) else Row:=MaxLinesPerPage;
  541.                             If Col<Length(AHelpRec.HelpLines[Row]) 
  542.                                                                then Inc(Col);
  543.                             Linked:=Find_Prev_Link(Col,Row,1,1,Ahelprec);
  544.                                     end;
  545.                            PgUp   : StackLvl:=Pop_Stack;
  546.                            PgDn   : Begin  {Let programmer set this!} end;
  547.                       end;
  548.                  end;
  549.            Until Ch=ESC;
  550.       end else
  551.       Writeln('ERROR: ',Result,' opening ',FileName,'. Unable to continue.');
  552.       {$I-} Close(HelpFile); result:=IOResult; {$I+}
  553.  end; {do help}
  554. {--------------------------------------------------------------------}
  555.  Begin {No init code required}
  556.  end.
  557.  
  558.  
  559. [EXAMPLE 1]
  560.  
  561.     Const    ScreenWidth = 60;
  562.         LinesPerScreen = 15;
  563.         MaxHotLinks = 25;  {Or any other number you want}
  564.  
  565.     Type       {heres a place to store the screen text}
  566.         ScreenTextBuffer = Array[  1..ScreenWidth, 
  567.                         1..LinesPerScreen] of Char;
  568.  
  569.         HotLinkRecord = Record    
  570.             Startpos,        {col pos where link occurs}
  571.             LineNum  : Integer; {row/line number where link occurs}
  572.             LinkPage : Integer;  {page number to activate for link}
  573.         end;
  574.  
  575.              {now put it all together}
  576.         OnePage = Record
  577.             TheText  : ScreenTextBuffer;
  578.             TheLinks : Array[1..MaxHotLinks] of HotLinkRecord;
  579.         end;
  580.  
  581.  
  582. [EXAMPLE 2]
  583.  
  584.     Const    MaxLinesPerPage = 15;
  585.         MaxLineWidth    = 60;
  586.     Type    Help_Record = Record
  587.             HelpLines : Array[1..MaxLinesPerPage] of                String[100]; {Leave room for links}
  588.         end;
  589.  
  590.  
  591. [EXAMPLE 3]
  592.  
  593.        Helplines[8] = [` OS Shell    Main Index ']  {As a string}
  594.  
  595.             =  [ $20,$20,$20,$20,           {As Hex}
  596.                  $4F, $53, $20, $53, $68, $6C, $6C]
  597.  
  598.  
  599. [EXAMPLE 4]
  600.  
  601.             =  [ $20,$20,$20,$20,      
  602.                    $CF, $D3, $A0, $D3, 
  603.                    $E8, $EC, $EC, $00,$05]
  604.  
  605.  
  606. [EXAMPLE 5] 
  607.  
  608. Helplines[8] = [` OS Shell    Main Index ']  
  609.                                 ^
  610.                               (Character 17)
  611.  
  612.  
  613. [EXAMPLE 6]
  614.  
  615. HelpLines[8] = [` OS Shell<xx>    Main Index '];
  616.                 ^     ^
  617.             (Hot link)   (Character 19) 
  618.  
  619.  
  620. [EXAMPLE 7]
  621.  
  622.      1 Program HelpTest;
  623.      2 Uses Crt,HyprHelp;
  624.      3 Var FileName : String[80];
  625.      4 Begin
  626.      5    ClrScr;
  627.      6    {If you want to save the current text screen, do it here.}
  628.      7    Write(TEnter the file name: U);
  629.      8    Readln(FileName);
  630.      9    Help_Editor( FileName );
  631.     10    Do_Help ( FileName,1,1);
  632.     11    { Restore the text screen here, if you saved it before }
  633.     12 end.
  634.  
  635.